home *** CD-ROM | disk | FTP | other *** search
/ Hardcore Visual Basic 5.0 (2nd Edition) / Hardcore Visual Basic 5.0 - Second Edition (1997)(Microsoft Press).iso / Code / LOCALM~1 / ModTool.bas < prev    next >
BASIC Source File  |  1997-06-14  |  24KB  |  645 lines

  1. Attribute VB_Name = "MModTool"
  2. Option Explicit
  3.  
  4. '$ Uses UTILITY.BAS DEBUG.BAS WINTOOL.BAS
  5.  
  6. '' ToolHelp functions for Windows 95 and Windows NT
  7.  
  8. ' Windows 95 Private Declares, constants, and Private Types
  9. ' Use the ToolHelp functions found in KERNEL32.DLL
  10.  
  11. Public Enum EErrorModTool
  12.     eeBaseModTool = 13530   ' ModTool
  13. End Enum
  14.  
  15. Const MAX_MODULE_NAME32 = 255
  16.  
  17. ' ****** Shapshot function *****
  18.  
  19. Private Declare Function CreateToolhelp32Snapshot Lib "KERNEL32" ( _
  20.     ByVal dwFlags As Long, ByVal th32ProcessID As Long) As Long
  21.  
  22. '
  23. ' The th32ProcessID argument is only used if TH32CS_SNAPHEAPLIST or
  24. ' TH32CS_SNAPMODULE is specified. th32ProcessID == 0 means the current
  25. ' process.
  26. '
  27. ' NOTE that all of the snapshots are global except for the heap and module
  28. '       lists which are process specific. To enumerate the heap or module
  29. '       state for all WIN32 processes call with TH32CS_SNAPALL and the
  30. '       current process. Then for each process in the TH32CS_SNAPPROCESS
  31. '       list that isn't the current process, do a call with just
  32. '       TH32CS_SNAPHEAPLIST and/or TH32CS_SNAPMODULE.
  33. '
  34. ' dwFlags
  35. '
  36. Const TH32CS_SNAPHEAPLIST = &H1&
  37. Const TH32CS_SNAPPROCESS = &H2&
  38. Const TH32CS_SNAPTHREAD = &H4&
  39. Const TH32CS_SNAPMODULE = &H8&
  40. Const TH32CS_SNAPALL = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or _
  41.                         TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)
  42. Const TH32CS_INHERIT = &H80000000
  43. '
  44. ' Use CloseHandle to destroy the snapshot
  45. '
  46.  
  47. ' ****** heap walking ******
  48. #If 0 Then  ' In Visual Basic? No way!
  49.  
  50. Private Type HEAPLIST32
  51.     dwSize As Long
  52.     th32ProcessID As Long    ' owning process
  53.     th32HeapID As Long       ' heap (in owning process's context!)
  54.     dwFlags As Long
  55. End Type
  56.  
  57. '
  58. ' dwFlags
  59. '
  60. Const HF32_DEFAULT = 1        ' process's default heap
  61. Const HF32_SHARED = 2         ' is shared heap
  62.  
  63. Private Declare Function Heap32ListFirst Lib "TOOLHELP32" ( _
  64.     ByVal hSnapshot As Long, lphl As HEAPLIST32) As Long
  65. Private Declare Function Heap32ListNext Lib "TOOLHELP32" ( _
  66.     ByVal hSnapshot As Long, lphl As HEAPLIST32) As Long
  67.  
  68. Private Type HEAPENTRY32
  69.     dwSize As Long
  70.     hHandle As Long         ' Handle of this heap block
  71.     dwAddress As Long       ' Linear address of start of block
  72.     dwBlockSize As Long     ' Size of block in bytes
  73.     dwFlags As Long
  74.     dwLockCount As Long
  75.     dwResvd As Long
  76.     th32ProcessID As Long   ' Owning process
  77.     th32HeapID As Long      ' Heap block is in
  78. End Type
  79.  
  80. '
  81. ' dwFlags
  82. '
  83. Const LF32_FIXED = &H1&
  84. Const LF32_FREE = &H2&
  85. Const LF32_MOVEABLE = &H4&
  86.  
  87. Private Declare Function Heap32First Lib "KERNEL32" (lphe As HEAPENTRY32, _
  88.     ByVal th32ProcessID As Long, ByVal th32HeapID As Long) As Long
  89. Private Declare Function Heap32Next Lib "KERNEL32" (lphe As HEAPENTRY32) As Long
  90. Private Declare Function Toolhelp32ReadProcessMemory Lib "KERNEL32" ( _
  91.     ByVal th32ProcessID As Long, ByVal lpBaseAddress As Long, _
  92.     ByVal lpBuffer As Long, ByVal cbRead As Long, _
  93.     lpNumberOfBytesRead As Long) As Long
  94. #End If
  95.  
  96. ' ***** Process walking ****
  97.  
  98. Private Type PROCESSENTRY32
  99.     dwSize As Long
  100.     cntUsage As Long
  101.     th32ProcessID As Long           ' This process
  102.     th32DefaultHeapID As Long
  103.     th32ModuleID As Long            ' Associated exe
  104.     cntThreads As Long
  105.     th32ParentProcessID As Long     ' This process's parent process
  106.     pcPriClassBase As Long          ' Base priority of process's threads
  107.     dwFlags As Long
  108.     szExeFile As String * 260       ' MAX_PATH
  109. End Type
  110.  
  111. Private Declare Function Process32First Lib "KERNEL32" ( _
  112.     ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
  113. Private Declare Function Process32Next Lib "KERNEL32" ( _
  114.     ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
  115.  
  116. ' ***** Thread walking *****
  117. #If 0 Then          ' Don't bother!
  118. Private Type THREADENTRY32
  119.     dwSize As Long
  120.     cntUsage As Long
  121.     th32ThreadID As Long        ' this thread
  122.     th32OwnerProcessID As Long  ' Process this thread is associated with
  123.     tpBasePri As Long
  124.     tpDeltaPri As Long
  125.     dwFlags As Long
  126. End Type
  127.  
  128. Private Declare Function Thread32First Lib "KERNEL32" ( _
  129.     ByVal hSnapshot As Long, lpte As THREADENTRY32) As Long
  130. Private Declare Function Thread32Next Lib "KERNEL32" ( _
  131.     ByVal hSnapshot As Long, lpte As THREADENTRY32) As Long
  132. #End If
  133.  
  134. ' ***** Module walking *****
  135.  
  136. Private Type MODULEENTRY32
  137.     dwSize As Long
  138.     th32ModuleID As Long        ' This module
  139.     th32ProcessID As Long       ' owning process
  140.     GlblcntUsage As Long        ' Global usage count on the module
  141.     ProccntUsage As Long        ' Module usage count in th32ProcessID's context
  142.     modBaseAddr As Long         ' Base address of module in th32ProcessID's context
  143.     modBaseSize As Long         ' Size in bytes of module starting at modBaseAddr
  144.     hModule As Long             ' The hModule of this module in th32ProcessID's context
  145.     szModule As String * 256    ' MAX_MODULE_NAME32 + 1
  146.     szExePath As String * 260   ' MAX_PATH
  147. End Type
  148.  
  149. '
  150. ' NOTE CAREFULLY that the modBaseAddr and hModule fields are valid ONLY
  151. ' in th32ProcessID's process context.
  152. '
  153.  
  154. Private Declare Function Module32First Lib "KERNEL32" ( _
  155.     ByVal hSnapshot As Long, lpme As MODULEENTRY32) As Long
  156. Private Declare Function Module32Next Lib "KERNEL32" ( _
  157.     ByVal hSnapshot As Long, lpme As MODULEENTRY32) As Long
  158.     
  159.  
  160. ' Windows NT Private Declares, constants, and Private Types
  161. ' Use the PSAPI functions found in PSAPI.DLL
  162.     
  163. Private Declare Function EnumProcesses Lib "PSAPI" ( _
  164.     lpidProcess As Long, ByVal cb As Long, cbNeeded As Long) As Long
  165.  
  166. Private Declare Function EnumProcessModules Lib "PSAPI" ( _
  167.     ByVal hProcess As Long, lphModule As Long, _
  168.     ByVal cb As Long, lpcbNeeded As Long) As Long
  169.  
  170. Private Declare Function GetModuleBaseName Lib "PSAPI" Alias "GetModuleBaseNameA" ( _
  171.     ByVal hProcess As Long, ByVal hModule As Long, _
  172.     ByVal lpBaseName As String, ByVal nSize As Long) As Long
  173.  
  174. Private Declare Function GetModuleBaseNameW Lib "PSAPI" ( _
  175.     ByVal hProcess As Long, ByVal hModule As Long, _
  176.     lpBaseName As Byte, ByVal nSize As Long) As Long
  177.  
  178. Private Declare Function GetModuleFileNameEx Lib "PSAPI" Alias "GetModuleFileNameExA" ( _
  179.     ByVal hProcess As Long, ByVal hModule As Long, _
  180.     ByVal lpFileName As String, ByVal nSize As Long) As Long
  181.  
  182. Private Declare Function GetModuleFileNameExW Lib "PSAPI" ( _
  183.     ByVal hProcess As Long, ByVal hModule As Long, _
  184.     lpFileName As Byte, ByVal nSize As Long) As Long
  185.  
  186. Private Type MODULEINFO
  187.     lpBaseOfDll As Long
  188.     SizeOfImage As Long
  189.     EntryPoint As Long
  190. End Type
  191.  
  192. Private Declare Function GetModuleInformation Lib "PSAPI" ( _
  193.     ByVal hProcess As Long, ByVal hModule As Long, _
  194.     lpmodinfo As MODULEINFO, ByVal cb As Long) As Long
  195.  
  196. ' Additional PSAPI functions that I don't use from Visual Basic
  197. #If 0 Then
  198. Private Declare Function EmptyWorkingSet Lib "PSAPI" ( _
  199.     ByVal hProcess As Long) As Long
  200.  
  201. Private Declare Function QueryWorkingSet Lib "PSAPI" ( _
  202.     ByVal hProcess As Long, ByVal pv As Long, _
  203.     ByVal cb As Long) As Long
  204.  
  205. Private Declare Function InitializeProcessForWsWatch Lib "PSAPI" ( _
  206.     ByVal hProcess As Long) As Long
  207.  
  208. Private Type PSAPI_WS_WATCH_INFORMATION
  209.     FaultingPc As Long
  210.     FaultingVa As Long
  211. End Type
  212.  
  213. Private Declare Function GetWsChanges Lib "PSAPI" ( _
  214.     ByVal hProcess As Long, _
  215.     lpWatchInfo As PSAPI_WS_WATCH_INFORMATION) As Long
  216.  
  217. Private Declare Function GetMappedFileNameA Lib "PSAPI" ( _
  218.     ByVal hProcess As Long, lpv As Long, _
  219.     lpFileName As Byte, ByVal nSize As Long) As Long
  220.  
  221. Private Declare Function GetMappedFileNameW Lib "PSAPI" ( _
  222.     ByVal hProcess As Long, lpv As Long, _
  223.     ByVal lpFileName As String, ByVal nSize As Long) As Long
  224.  
  225. Private Declare Function EnumDeviceDrivers Lib "PSAPI" ( _
  226.     ByVal lpImageBase As Long, ByVal cb As Long, _
  227.     lpcbNeeded As Long) As Long
  228.  
  229. Private Declare Function GetDeviceDriverBaseNameA Lib "PSAPI" ( _
  230.     ByVal lpImageBase As Long, ByVal lpBaseName As String, _
  231.     ByVal nSize As Long) As Long
  232.  
  233. Private Declare Function GetDeviceDriverBaseNameW Lib "PSAPI" ( _
  234.     ByVal lpImageBase As Long, lpBaseName As Byte, _
  235.     ByVal nSize As Long) As Long
  236.  
  237. Private Declare Function GetDeviceDriverFileNameA Lib "PSAPI" ( _
  238.     ByVal lpImageBase As Long, ByVal lpFileName As String, _
  239.     ByVal nSize As Long) As Long
  240.  
  241. Private Declare Function GetDeviceDriverFileNameW Lib "PSAPI" ( _
  242.     ByVal lpImageBase As Long, lpFileName As Byte, _
  243.     ByVal nSize As Long) As Long
  244.  
  245. ' Structure for GetProcessMemoryInfo()
  246.  
  247. Private Type PROCESS_MEMORY_COUNTERS
  248.     cb As Long
  249.     PageFaultCount As Long
  250.     PeakWorkingSetSize As Long
  251.     WorkingSetSize As Long
  252.     QuotaPeakPagedPoolUsage As Long
  253.     QuotaPagedPoolUsage As Long
  254.     QuotaPeakNonPagedPoolUsage As Long
  255.     QuotaNonPagedPoolUsage As Long
  256.     PagefileUsage As Long
  257.     PeakPagefileUsage As Long
  258. End Type
  259.  
  260. Private Declare Function GetProcessMemoryInfo Lib "PSAPI" ( _
  261.     ByVal hProcess As Long, ppsmemCounters As PROCESS_MEMORY_COUNTERS, _
  262.     ByVal cb As Long) As Long
  263. #End If
  264.  
  265. Function CreateProcessList() As CVector
  266.     Dim c As Long, f As Long, sName As String
  267.     Dim vec As CVector, process As CProcess
  268.     Set vec = New CVector
  269.     
  270.     If MUtility.IsNT = False Then
  271.         ' Windows 95 uses ToolHelp32 functions
  272.         Dim hSnap As Long, proc As PROCESSENTRY32
  273.         ' Take a picture of current process list
  274.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  275.         If hSnap = hNull Then Exit Function
  276.         proc.dwSize = Len(proc)
  277.         ' Iterate through the processes
  278.         f = Process32First(hSnap, proc)
  279.         Do While f
  280.             ' Put this process in vector and count it
  281.             sName = MUtility.StrZToStr(proc.szExeFile)
  282.             Set process = New CProcess
  283.             process.Create proc.th32ProcessID, MUtility.GetFileBaseExt(sName)
  284.             c = c + 1
  285.             Set vec(c) = process
  286.             f = Process32Next(hSnap, proc)
  287.         Loop
  288.     Else
  289.         ' Windows NT uses PSAPI functions
  290.         Dim i As Long, iCur As Long, cRequest As Long, cGot As Long
  291.         Dim aProcesses() As Long, hProcess As Long, hModule As Long
  292.         cRequest = 96       ' Request in bytes for 24 processes
  293.         Do
  294.             ReDim aProcesses(0 To (cRequest / 4) - 1) As Long
  295.             f = EnumProcesses(aProcesses(0), cRequest, cGot)
  296.             If f = 0 Then Exit Function
  297.             If cGot < cRequest Then Exit Do
  298.             cRequest = cRequest * 2
  299.         Loop
  300.         cGot = cGot / 4     ' From bytes to processes
  301.         ReDim Preserve aProcesses(0 To cGot - 1) As Long
  302.         
  303.         For i = 0 To cGot - 1
  304.             hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  305.                                    PROCESS_VM_READ, 0, _
  306.                                    aProcesses(i))
  307.             ' Ignore processes that fail (probably no
  308.             ' security rights)
  309.             If hProcess = 0 Then GoTo NextFor
  310.             ' Get first module only
  311.             f = EnumProcessModules(hProcess, hModule, 4, c)
  312.             If f = 0 Then GoTo NextFor
  313.             sName = String$(cMaxPath, 0)
  314.             c = GetModuleFileNameEx(hProcess, hModule, sName, cMaxPath)
  315.             ' Put this process in vector and count it
  316.             Set process = New CProcess
  317.             process.Create aProcesses(i), Left$(sName, c)
  318.             iCur = iCur + 1
  319.             Set vec(iCur) = process
  320. NextFor:
  321.         Next
  322.     End If
  323.     Set CreateProcessList = vec
  324. End Function
  325.  
  326. Function CreateModuleList(idProcessA As Long) As CVector
  327.     Dim sName As String, f As Long, c As Long, i As Long, iCur As Long
  328.     Dim vec As CVector, module As CModule
  329.     Set vec = New CVector
  330.     
  331.     If MUtility.IsNT = False Then
  332.         ' Windows 95 uses ToolHelp functions
  333.         Dim modu As MODULEENTRY32, hSnap As Long
  334.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProcessA)
  335.         If hSnap = hNull Then Exit Function
  336.         modu.dwSize = Len(modu)
  337.         f = Module32First(hSnap, modu)
  338.         Do While f
  339.             Set module = New CModule
  340.             sName = MUtility.GetFileBaseExt(MUtility.StrZToStr(modu.szExePath))
  341.             ' Validate module handle
  342.             If sName = ExeNameFromMod(modu.hModule) Then
  343.                 module.Create modu.th32ProcessID, modu.modBaseAddr, sName
  344.                 i = i + 1
  345.                 Set vec(i) = module
  346.             End If
  347.             f = Module32Next(hSnap, modu)
  348.         Loop
  349.     Else
  350.         ' Windows NT uses PSAPI functions
  351.         Dim cRequest As Long, cGot As Long
  352.         Dim aModules() As Long, hProcess As Long, hModule As Long
  353.         ' Get a handle
  354.         hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  355.                                PROCESS_VM_READ, 0, idProcessA)
  356.         If hProcess = 0 Then Exit Function
  357.         cRequest = 48       ' Request in bytes (16 modules)
  358.         Do
  359.             ReDim aModules(0 To (cRequest / 4) - 1) As Long
  360.             f = EnumProcessModules(hProcess, aModules(0), cRequest, cGot)
  361.             If f = 0 Then Exit Function
  362.             If cGot < cRequest Then Exit Do
  363.             cRequest = cRequest * 2
  364.         Loop
  365.         cGot = cGot / 4     ' From bytes to modules
  366.         ReDim Preserve aModules(0 To cGot - 1) As Long
  367.  
  368.         For i = 0 To cGot - 1
  369.             sName = String$(cMaxPath, 0)
  370.             c = GetModuleFileNameEx(hProcess, aModules(i), sName, cMaxPath)
  371.             If c = 0 Then GoTo NextFor
  372.             sName = Left$(sName, c)
  373.             Set module = New CModule
  374.             module.Create idProcessA, aModules(i), sName
  375.             iCur = iCur + 1
  376.             Set vec(iCur) = module
  377. NextFor:
  378.         Next
  379.     End If
  380.     Set CreateModuleList = vec
  381. End Function
  382.  
  383. Function ExeNameFromMod(ByVal hMod As Long) As String
  384.     Dim sT As String, cT As Long
  385.     cT = 256: sT = String$(256, 0)
  386.     cT = GetModuleFileName(hMod, sT, cT)
  387.     sT = Left$(sT, cT)
  388.     ExeNameFromMod = MUtility.GetFileBaseExt(sT)
  389. End Function
  390.  
  391. Function ModFromWnd(ByVal hWnd As Long) As Long
  392.     BugAssert hWnd <> hNull
  393.     ModFromWnd = ModFromProcID(MWinTool.ProcIDFromWnd(hWnd))
  394. End Function
  395.  
  396. Function ModFromProcID(ByVal idProc As Long) As Long
  397.     If Not MUtility.IsNT Then
  398.         Dim process As PROCESSENTRY32, module As MODULEENTRY32
  399.         Dim hSnap As Long, f As Long, idModule As Long
  400.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  401.         If hSnap = hNull Then Exit Function
  402.         ' Loop through to find matching process
  403.         process.dwSize = Len(process)
  404.         f = Process32First(hSnap, process)
  405.         Do While f
  406.             If process.th32ProcessID = idProc Then
  407.                 ' Save module ID
  408.                 idModule = process.th32ModuleID
  409.                 Exit Do
  410.             End If
  411.             f = Process32Next(hSnap, process)
  412.         Loop
  413.         
  414.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProc)
  415.         If hSnap = hNull Then Exit Function
  416.         ' Loop through to find matching module
  417.         module.dwSize = Len(module)
  418.         f = Module32First(hSnap, module)
  419.         Do While f
  420.             If module.th32ModuleID = idModule Then
  421.                 ModFromProcID = module.hModule
  422.                 Exit Function
  423.             End If
  424.             f = Module32Next(hSnap, module)
  425.         Loop
  426.     Else
  427.         Dim hModule As Long, c As Long
  428.         ' First module is the main executable
  429.         f = EnumProcessModules(ProcFromProcID(idProc), hModule, 4, c)
  430.         ' Ignore errors (probably you have no security access)
  431.         If f Then ModFromProcID = hModule
  432.     End If
  433. End Function
  434.  
  435. Function InstFromProcID(ByVal idProc As Long) As String
  436.     Dim f As Long, hModule As Long, c As Long
  437.     If Not MUtility.IsNT Then
  438.         Dim process As PROCESSENTRY32, module As MODULEENTRY32
  439.         Dim hSnap As Long, idModule As Long
  440.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  441.         If hSnap = hNull Then Exit Function
  442.         ' Loop through to find matching process
  443.         process.dwSize = Len(process)
  444.         f = Process32First(hSnap, process)
  445.         Do While f
  446.             If process.th32ProcessID = idProc Then
  447.                 ' Save module ID
  448.                 idModule = process.th32ModuleID
  449.                 Exit Do
  450.             End If
  451.             f = Process32Next(hSnap, process)
  452.         Loop
  453.         
  454.         ' Loop through modules
  455.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProc)
  456.         If hSnap = hNull Then Exit Function
  457.         module.dwSize = Len(module)
  458.         f = Module32First(hSnap, module)
  459.         Do While f
  460.             If module.th32ModuleID = idModule Then
  461.                 InstFromProcID = module.modBaseAddr
  462.                 Exit Function
  463.             End If
  464.             f = Module32Next(hSnap, module)
  465.         Loop
  466.     Else
  467.         ' First module is the main executable
  468.         f = EnumProcessModules(ProcFromProcID(idProc), hModule, 4, c)
  469.         If f = 0 Then Exit Function
  470.         Dim modinfo As MODULEINFO
  471.         f = GetModuleInformation(ProcFromProcID(idProc), hModule, modinfo, c)
  472.         If f Then InstFromProcID = modinfo.lpBaseOfDll
  473.     End If
  474. End Function
  475.  
  476. Function ProcIDFromInst(ByVal hInst As Long) As String
  477.     Dim f As Long, c As Long, idProc As Long
  478.     If Not MUtility.IsNT Then
  479.         Dim process As PROCESSENTRY32, hSnap As Long
  480.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  481.         If hSnap = hNull Then Exit Function
  482.         process.dwSize = Len(process)
  483.         f = Process32First(hSnap, process)
  484.         Do While f
  485.             If InstFromProcID(process.th32ProcessID) = hInst Then
  486.                 ProcIDFromInst = process.th32ProcessID
  487.                 Exit Function
  488.             End If
  489.             f = Process32Next(hSnap, process)
  490.         Loop
  491.     Else
  492.         Dim i As Long, iCur As Long, cRequest As Long, cGot As Long, modinfo As MODULEINFO
  493.         Dim aProcesses() As Long, hProcess As Long, hModule As Long
  494.         cRequest = 96       ' Request in bytes (32 processes)
  495.         Do
  496.             ReDim aProcesses(0 To (cRequest / 4) - 1) As Long
  497.             f = EnumProcesses(aProcesses(0), cRequest, cGot)
  498.             If f = 0 Then Exit Function
  499.             If cGot < cRequest Then Exit Do
  500.             cRequest = cRequest * 2
  501.         Loop
  502.         cGot = cGot / 4     ' From bytes to processes
  503.         ReDim Preserve aProcesses(0 To cGot - 1) As Long
  504.         
  505.         For i = 0 To cGot - 1
  506.             hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  507.                                    PROCESS_VM_READ, 0, aProcesses(i))
  508.             ' Ignore processes that fail (probably don't have security rights)
  509.             If hProcess = 0 Then GoTo NextFor
  510.             ' Get first module only
  511.             f = EnumProcessModules(hProcess, hModule, 4, c)
  512.             If f = 0 Then GoTo NextFor
  513.             f = GetModuleInformation(ProcFromProcID(idProc), hModule, modinfo, c)
  514.             If f = 0 Then GoTo NextFor
  515.             ProcIDFromInst = modinfo.lpBaseOfDll
  516.             iCur = iCur + 1
  517. NextFor:
  518.         Next
  519.     End If
  520. End Function
  521.  
  522. Function ProcFromInst(ByVal hInst As Long) As String
  523.     ProcFromInst = ProcIDFromInst(hInst)
  524. End Function
  525.  
  526. Function ModFromInst(ByVal hInst As Long) As String
  527.     ModFromInst = ModFromProcID(ProcIDFromInst(hInst))
  528. End Function
  529.  
  530. Function ProcFromProcID(idProc As Long)
  531.     ProcFromProcID = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  532.                                  PROCESS_VM_READ, 0, idProc)
  533. End Function
  534.  
  535. Function ExeNameFromWnd(ByVal hWnd As Long) As String
  536.     BugAssert hWnd <> hNull
  537.     ExeNameFromWnd = MUtility.GetFileBaseExt(ExePathFromWnd(hWnd))
  538. End Function
  539.  
  540. Function ExePathFromWnd(ByVal hWnd As Long) As String
  541.     ExePathFromWnd = ExePathFromProcID(MWinTool.ProcIDFromWnd(hWnd))
  542. End Function
  543.  
  544. Function ExePathFromProcID(idProc As Long) As String
  545.     If Not MUtility.IsNT Then
  546.         Dim process As PROCESSENTRY32, hSnap As Long, f As Long
  547.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  548.         If hSnap = hNull Then Exit Function
  549.         process.dwSize = Len(process)
  550.         f = Process32First(hSnap, process)
  551.         Do While f
  552.             If process.th32ProcessID = idProc Then
  553.                 ExePathFromProcID = MUtility.StrZToStr(process.szExeFile)
  554.                 Exit Function
  555.             End If
  556.             f = Process32Next(hSnap, process)
  557.         Loop
  558.     Else
  559.         Dim s As String, c As Long
  560.         s = String$(cMaxPath, 0)
  561.         c = GetModuleFileNameEx(ProcFromProcID(idProc), _
  562.                                 ModFromProcID(idProc), s, cMaxPath)
  563.         If c Then ExePathFromProcID = Left$(s, c)
  564.     End If
  565. End Function
  566.  
  567. Function ExeNameFromProcID(idProc As Long) As String
  568.     ExeNameFromProcID = MUtility.GetFileBaseExt(ExePathFromProcID(idProc))
  569. End Function
  570.  
  571. Function ModFromExePath(sExe As String) As Long
  572.     ModFromExePath = GetModuleHandle(sExe)
  573. End Function
  574.  
  575. Function GetFirstInstWnd(hWndMe As Long) As Long
  576.     Dim hWndYou As Long, idMe As Long, sExeMe As String
  577.     
  578.     ' Get my own process ID and executable name
  579.     idMe = MWinTool.ProcIDFromWnd(hWndMe)
  580.     sExeMe = ExeNameFromWnd(hWndMe)
  581.     ' Get first sibling to start iterating top-level windows
  582.     hWndYou = GetWindow(hWndMe, GW_HWNDFIRST)
  583.     Do While hWndYou <> hNull
  584.         ' Ignore if process ID of target is same
  585.         If idMe <> MWinTool.ProcIDFromWnd(hWndYou) Then
  586.             ' Ignore if module name is different
  587.             If sExeMe = ExeNameFromWnd(hWndYou) Then
  588.                 ' Return first with same module, different process
  589.                 GetFirstInstWnd = hWndYou
  590.                 Exit Function
  591.             End If
  592.         End If
  593.         ' Get next sibling
  594.         hWndYou = GetWindow(hWndYou, GW_HWNDNEXT)
  595.     Loop
  596. End Function
  597.  
  598. Function GetAllInstWnd(hWndMe As Long) As CVector
  599.     Dim hWndYou As Long, idMe As Long, sExeMe As String
  600.     Dim vecWnds As CVector, i As Long
  601.     Set vecWnds = New CVector
  602.     
  603.     ' Get my own process ID and executable name
  604.     idMe = MWinTool.ProcIDFromWnd(hWndMe)
  605.     sExeMe = ExeNameFromWnd(hWndMe)
  606.     ' Get first sibling to start iterating top level windows
  607.     hWndYou = GetWindow(hWndMe, GW_HWNDFIRST)
  608.     Do While hWndYou <> hNull
  609.         ' Ignore if process ID of target is same
  610.         If idMe <> MWinTool.ProcIDFromWnd(hWndYou) Then
  611.             ' Ignore if module name is different
  612.             If sExeMe = ExeNameFromWnd(hWndYou) Then
  613.                 ' Return all with same module, different process
  614.                 i = i + 1
  615.                 vecWnds(i) = hWndYou
  616.             End If
  617.         End If
  618.         ' Get next sibling
  619.         hWndYou = GetWindow(hWndYou, GW_HWNDNEXT)
  620.     Loop
  621.     Set GetAllInstWnd = vecWnds
  622. End Function
  623. '
  624.  
  625. #If fComponent = 0 Then
  626. Private Sub ErrRaise(e As Long)
  627.     Dim sText As String, sSource As String
  628.     If e > 1000 Then
  629.         sSource = App.ExeName & ".ModTool"
  630.         Select Case e
  631.         Case eeBaseModTool
  632.             BugAssert True
  633.        ' Case ee...
  634.        '     Add additional errors
  635.         End Select
  636.         Err.Raise COMError(e), sSource, sText
  637.     Else
  638.         ' Raise standard Visual Basic error
  639.         sSource = App.ExeName & ".VBError"
  640.         Err.Raise e, sSource
  641.     End If
  642. End Sub
  643. #End If
  644.  
  645.